home *** CD-ROM | disk | FTP | other *** search
- ****************************************************************************
- *
- * Let 'em Fly! V1.2 Installing & Trap Part
- *
- * (c) 1991-92 by Oliver Scheel
- *
- ****************************************************************************
-
- import nap_exit,load_icons,get_cookie
-
- import nfm_dial,nfm_do,nfm_button,nfm_keybd,nfm_center
- import nfm_alert,nfm_error
- import nob_edit
- import menu_patch,niceline,init_niceline,nl_handle
-
- import netv_critic
-
- import di_fly,obj_clsize,init_keys,lookup_key
- import di_moveto,ins_spcchar,hist_insert,di_center
- import dialno,lasttree,lastdone,was_used
-
- import vers,cpyright
- import aes,global
-
- export letemfly
- export mousecnt,jacks_in,magx,aes_version
-
- export new_trap2,old_trap2
-
- ****************************************************************************
-
- LIGHT equ 0
- ETV_CRITIC equ 1
-
- XBRA_ID equ 'LTMF'
-
- ****************************************************************************
-
- trap2v equ $88 ; AES/VDI Trap
- trap13v equ $b4 ; BIOS Trap
-
- RESMAGIC EQU $31415926
- _resvalid EQU $0426
- _resvector EQU $042a
-
- etv_critic EQU $0404
-
- _p_cookies EQU $05a0
-
- savptr EQU $04a2
- _sysbase EQU $04f2
-
- MAXCOOKIE EQU 20
-
- ****************************************************************************
-
- CFG_BYPASS equ 0
- CFG_G_GROW equ 1
- CFG_ALERT equ 4
-
- CFG_NICELN equ 6
-
- ****************************************************************************
-
- text
-
- ****************************************************************************
- * install
- ****************************************************************************
-
- start:
- movea.l 4(sp),a0 ; basepage address
- move.l #$100,a6 ; basepage lenght
- add.l 12(a0),a6 ; add textlen
- add.l 20(a0),a6 ; add datalen
- add.l 28(a0),a6 ; add bsslen
- move.l a6,prglen ; save length
- move.l a0,prgstart ; save prgstart
-
- lea my_stack,sp
-
- move.l a6,-(sp) ; new length
- move.l a0,-(sp) ; beginning of block
- clr.w -(sp) ; dummy
- move.w #$4a,-(sp) ; Mshrink()
- trap #1 ; GEMDOS
- lea 12(sp),sp
-
- bsr vq_aes
- tst.w d0 ; AES already aktive ?
- beq skip2 ; no -> skip
- move.w #1,gem_inst
-
- skip2:
- lea rvs_on,a0 ; reverse on
- bsr strout
- move.l vers,a0 ; version
- addq.l #4,a0
- bsr strout
- lea rvs_off,a0 ; reverse off
- bsr strout
- move.l cpyright,a0 ; copyright
- bsr strout
- lea freaky,a0 ; Freaky Deaky
- bsr strout
-
- pea install ; install new routines
- move.w #38,-(sp) ; Supexec()
- trap #14 ; XBIOS
- addq.l #6,sp
- tst.w d0 ; test result
- bne skip3 ; fault -> cancel
-
- .iff LIGHT
- jsr load_icons(pc) ; load icons
- tst.w d0 ; test result
- beq skip5 ; FALSE -> no icons loaded
- lea ld_icons,a0 ; TRUE -> print message
- bsr strout
- .endif
- skip5:
- pea new_trap13 ; install TRAP #13 (BIOS)
- move.w #45,-(sp) ; Exeption 45
- move.w #5,-(sp) ; Setexc()
- trap #13
- addq.l #8,sp
- move.l d0,old_trap13 ; save old vector
-
- tst.w gem_inst ; AES isntalled
- beq skip4 ; no -> skip
-
- pea new_trap2 ; install TRAP #2 (AES)
- move.w #34,-(sp) ; Exeption 34
- move.w #5,-(sp) ; Setexc()
- trap #13
- addq.l #8,sp
- move.l d0,old_trap2 ; save old vector
-
- skip4:
- .if ETV_CRITIC
- move.l #'MagX',d0 ; looking for clues
- jsr get_cookie(pc)
- move.l a0,magx
- bne skip6 ; Mag!X available
- bra skip1
-
- /* move.l #'MiNT',d0
- jsr get_cookie(pc)
- cmp.l #0,a0
- beq skip1
- */
- skip6: move.l a0,multi_aes
- pea new_etv_critic ; install etv_critic handler
- move.w #257,-(sp) ; Exception 257
- move.w #5,-(sp) ; Setexc()
- trap #13
- addq.l #8,sp
- move.l d0,old_etv_critic ; save old vector
- .endif
-
-
- skip1: clr.w -(sp)
- move.l prglen,-(sp) ; length onto stack
- move.w #$31,-(sp) ; for Ptermres()
- trap #1 ; GEMDOS
-
- skip3: lea double_err,a0 ; already installed
- bsr strout
-
- clr.w -(sp) ; Pterm0()
- trap #1 ; GEMDOS
-
- ****************************************************************************
-
- install:
- move.l _sysbase,os_start ; get os_start
-
- tst.l _p_cookies ; cookie-jar already alive ?
- bne in_skip1 ; yes -> go on
- bsr inst_cookie ; no -> install the jar
-
- in_skip1: movea.l _p_cookies,a0 ; get cookie-jar base
- moveq #1,d0 ; clear counter
- cookloop: tst.l (a0) ; free entry ?
- beq cookexit ; yes -> install cookie id
- cmpi.l #XBRA_ID,(a0) ; LTMF alread installed ?
- beq already_in ; yes -> quit
- addq.l #8,a0
- addq.l #1,d0
- bne cookloop ; no -> next
- cookexit: cmp.l 4(a0),d0 ; cookie-jar full ?
- bne cookskip ; no -> install it
- bsr copycookie ; copy cookie-jar
- cookskip: move.l (a0),8(a0) ; copy last cookie
- move.l 4(a0),12(a0)
- move.l #XBRA_ID,(a0)+ ; cookie id
- move.l #letemfly,(a0) ; adress of structure
-
- tst.w $059e ; set stackcorr
- beq in_skip2
- move.l #8,stackcorr ; no 68000
- bra in_ok
- in_skip2: move.l #6,stackcorr ; only a 68000
-
- in_ok: moveq #0,d0 ; o.k.
- rts
-
- already_in: moveq #-1,d0 ; error
- rts
-
- ****************************************************************************
- * install cookie-jar
- ****************************************************************************
-
- inst_cookie:
- lea cookiejar,a0
- move.l a0,_p_cookies ; adress to _p_cookies
- clr.l (a0)+ ; make 'last cookie'
- move.l #MAXCOOKIE,(a0)
-
- move.l _resvalid,old_rvalid ; install new reset-routine
- move.l #RESMAGIC,_resvalid
- move.l _resvector,old_reset
- move.l #new_reset,_resvector
-
- rts
-
- ****************************************************************************
- * copy cookie-jar
- ****************************************************************************
-
- copycookie:
- movea.l _p_cookies.w,a1 ; save old address
- bsr inst_cookie ; install new cookie-jar
- movea.l _p_cookies.w,a0 ; get new address
- cpcook_loop: move.l (a1)+,(a0)+ ; copy cookie
- move.l (a1)+,(a0)+
- tst.l (a1) ; last cookie ?
- bne cpcook_loop ; no -> next cookie
- clr.l (a0) ; make 'last cookie'
- move.l #MAXCOOKIE,4(a0)
- rts
-
- *******************************************************************************
- * new reset routine (deletes the cookie jar)
- *******************************************************************************
-
- dc.b 'XBRA'
- dc.l XBRA_ID
- old_reset: dc.l 0
-
- new_reset: clr.l _p_cookies ; clear cookie-jar
- move.l old_reset,_resvector
- move.l old_rvalid,_resvalid
- jmp (a6)
-
- ****************************************************************************
- * vq_aes
- ****************************************************************************
-
- vq_aes:
- move.w #$0a,d0 ; appl_init()
- jsr aes
- move.w global,d0 ; is GEM out there?
- rts
-
- ****************************************************************************
- * strout
- ****************************************************************************
-
- strout: tst.w gem_inst
- bne strout_exit
- move.l a0,-(sp) ; string
- move.w #9,-(sp) ; Cconws()
- trap #1 ; GEMDOS
- addq.l #6,sp
- strout_exit: rts
-
- ****************************************************************************
- ****************************************************************************
-
- ****************************************************************************
- * new TRAP #2 (AES/VDI)
- ****************************************************************************
-
- dc.b 'XBRA'
- dc.l XBRA_ID
- old_trap2: dc.l 0
-
- new_trap2:
- movem.l d2-d3/a1-a3,-(sp) ; save regs
- cmpi.w #$c8,d0 ; AES Call ?
- bne ntrp2_bypass ; no -> go to end
-
- movea.l d1,a2 ; AES parameter block
- movea.l (a2),a1 ; get contrl
- move.w (a1),d2 ; get func. no.
-
- btst #CFG_BYPASS,ltmf_config+1 ; BYPASS set ?
- beq ntrp2_skip ; no -> skip
- tst.w jacks_in ; second call ?
- bne ntrp2_bypass ; yes -> bypass
- cmpi.w #19,d2 ; appl_exit ?
- bne ntrp2_bypass ; no -> go to end
- move.l #ap_exit,aes_jump ; save adress
- bra my_aes ; and go
-
- ntrp2_skip: tst.w jacks_in ; second call ?
- bne ntrp2_bypass ; yes -> cancel
- ; bne nt2_skp1 ; yes -> check grow/shrink
-
- lea aes_tab,a3 ; get tab base
- moveq.l #0,d3 ; clear counter
- nt2_loop: tst.w (a3,d3.w) ; end of table ?
- beq nt2_skp1 ; yes -> cancel
- cmp.w (a3,d3.w),d2 ; = function no. ?
- beq nt2_skp2 ; yes -> go for it
- addq.w #6,d3 ; next entry
- bra nt2_loop ; and go
-
- nt2_skp2: move.l 2(a3,d3.w),aes_jump ; save adress
- bra my_aes
-
- nt2_skp1: cmpi.w #42,d2 ; objc_draw ?
- beq ob_draw
- cmpi.w #43,d2 ; objc_find ?
- beq ob_find
- cmpi.w #73,d2 ; graf_growbox ?
- beq gr_grow
- cmpi.w #74,d2 ; graf_shrinkbox ?
- beq gr_shrink
- cmpi.w #77,d2 ; graf_handle ?
- beq gr_handle
- cmpi.w #78,d2 ; graf_mouse ?
- beq gr_mouse
- cmpi.w #10,d2 ; appl_init() ?
- beq ap_init
- cmpi.w #30,d2 ; menu_bar() ?
- beq mn_bar
- cmpi.w #34,d2 ; menu_text() ?
- beq mn_text
-
- ntrp2_bypass: movem.l (sp)+,d2-d3/a1-a3 ; restore regs
- move.l old_trap2(pc),-(sp) ; old routine onto stack
- rts
-
- ****************************************************************************
-
- aes_tab: dc.w 50
- dc.l fm_do
- dc.w 51
- dc.l fm_dial
- .iff LIGHT
- dc.w 52
- dc.l fm_alert
- dc.w 53
- dc.l fm_error
- .endif
- dc.w 54
- dc.l fm_center
- dc.w 55
- dc.l fm_keybd
- dc.w 56
- dc.l fm_button
- dc.w 46
- dc.l ob_edit
- dc.w 19
- dc.l ap_exit
- dc.w 0
-
- ****************************************************************************
-
- my_aes:
- movem.l (sp)+,d2-d3/a1-a3 ; restore regs
- move.w (sp)+,d0 ; save SR from TRAP
- move.l (sp)+,ret_sav ; save return adress
- pea do_aes ; push my routine
- move.w d0,-(sp) ; SR back onto stack
- rte
-
- do_aes:
- move.w #1,jacks_in ; we are here
- move.l a0,tempsave ; save A0
- move.l sp,a0 ; get stack pointer
- move.l #my_stack-4,sp ; install new stack
- move.l a0,-(sp) ; save stack pointer
- movem.l d1-d7/a1-a6,-(sp) ; save regs
- move.l d1,a2 ; AES Parameter Block
- move.l aes_jump,a1 ; get adress
- jsr (a1) ; jump to routine
-
- move.l 12(a2),a0 ; int_out
- move.w d0,(a0) ; put result
-
- clr.w jacks_in ; now we'll go
-
- movem.l (sp)+,d1-d7/a1-a6 ; restore regs
- move.l (sp)+,sp ; restore stack pointer
- move.l tempsave,a0 ; restore A0
- move.l ret_sav,-(sp) ; return adress and go
- rts
-
- ****************************************************************************
-
- fm_do:
- movea.l 8(a2),a3 ; int_in
- move.w (a3),d0 ; start_obj
- movea.l 16(a2),a3 ; addr_in
- movea.l (a3),a0 ; *tree
- jmp nfm_do(pc) ; go for it
-
- ****************************************************************************
-
- fm_dial:
- movea.l 8(a2),a3 ; int_in
- move.w 16(a3),-(sp) ; h
- move.w 14(a3),-(sp) ; w
- move.w 12(a3),-(sp) ; y
- move.w 10(a3),-(sp) ; x
- move.w 8(a3),-(sp) ; hs
- move.w 6(a3),-(sp) ; ws
- move.w 4(a3),d2 ; ys
- move.w 2(a3),d1 ; xs
- move.w (a3),d0 ; flag
- jsr nfm_dial(pc) ; go for it
- lea 12(sp),sp
- rts
-
- ****************************************************************************
-
- .iff LIGHT
-
- fm_alert:
- movea.l 8(a2),a3 ; int_in
- move.w (a3),d0 ; button
- movea.l 16(a2),a3 ; addr_in
- movea.l (a3),a0 ; *string
- jmp nfm_alert(pc) ; go for it
-
- ****************************************************************************
-
- fm_error:
- movea.l 8(a2),a3 ; int_in
- move.w (a3),d0 ; error no.
- jmp nfm_error(pc) ; go for it
-
- .endif
-
- ****************************************************************************
-
- fm_center:
- movea.l 12(a2),a3 ; int_out
- pea 8(a3) ; fo_ch
- pea 6(a3) ; fo_cw
- pea 4(a3) ; fo_cy
- lea 2(a3),a1 ; fo_cx
- movea.l 16(a2),a3 ; addr_in
- movea.l (a3),a0 ; *tree
- jsr nfm_center(pc) ; go for it
- lea 12(sp),sp
- rts
-
- ****************************************************************************
-
- fm_keybd:
- movea.l 12(a2),a3 ; int_out
- lea 2(a3),a1 ; pchar
- pea 4(a3) ; pnxt_obj
- movea.l 8(a2),a3 ; int_in
- move.w 2(a3),d2 ; char
- move.w 4(a3),d1 ; next_obj
- move.w (a3),d0 ; obj
- movea.l 16(a2),a3 ; addr_in
- movea.l (a3),a0 ; *tree
- jsr nfm_keybd(pc) ; go for it
- addq.l #4,sp
- rts
-
- ****************************************************************************
-
- fm_button:
- movea.l 12(a2),a3 ; int_out
- lea 2(a3),a1 ; pnxt_obj
- movea.l 8(a2),a3 ; int_in
- move.w 2(a3),d1 ; clicks
- move.w (a3),d0 ; obj
- movea.l 16(a2),a3 ; addr_in
- movea.l (a3),a0 ; *tree
- jmp nfm_button(pc) ; go for it
-
- ****************************************************************************
-
- ob_edit:
- movea.l 8(a2),a3 ; int_in
- move.w 4(a3),d3 ; idx
- move.w 6(a3),d2 ; kind
- move.w 2(a3),d1 ; char
- move.w (a3),d0 ; obj
- movea.l 12(a2),a3 ; int_out
- lea 2(a3),a1 ; *idx
- move.w d3,(a1) ; put idx
- movea.l 16(a2),a3 ; addr_in
- movea.l (a3),a0 ; *tree
- jmp nob_edit(pc) ; go for it
-
- ****************************************************************************
-
- ap_init:
- ; tst.w aes_version ; already checked?
- ; bne ntrp2_bypass ; no -> quit
-
- move.w #1,jacks_in ; we are here
- move.l 4(a2),global_base
- movem.l (sp)+,d2-d3/a1-a3 ; restore regs
- move.w (sp)+,tempsave
- move.l (sp)+,ret_sav ; save return adress
- pea get_global ; my return adress
- move.w tempsave,-(sp)
- move.l old_trap2(pc),-(sp) ; old routine onto stack
- rts
-
- get_global:
- movem.l a0-a1/d2,-(sp) ; save regs
- move.l global_base,a0 ; global
- lea global,a1 ; my global
- /* moveq #6,d2 ; load counter
- api_loop: move.l (a0)+,(a1)+ ; copy global field
- dbra d2,api_loop ; next one
- move.w (a0),(a1) ; copy last word
- */
- tst.w (a0)
- beq api_skip
- move.w (a0),(a1) ; copy global[0]
- move.w (a0),aes_version
- api_skip: movem.l (sp)+,a0-a1/d2 ; restore regs
- move.l ret_sav,-(sp)
- clr.w jacks_in
- rts
-
- ****************************************************************************
-
- ap_exit:
- jmp nap_exit(pc) ; go for it
-
- ****************************************************************************
-
- ob_draw:
- movea.l 8(a2),a1 ; int_in
- cmpi.w #1,(a1)
- beq draw_menu
- tst.w (a1) ; test obj ROOT ?
- bne ntrp2_bypass ; no -> cancel
- movea.l 16(a2),a1 ; addr_in
- move.l (a1),lasttree ; save tree
- clr.l lastdone ; clear lastdone
- move.w #1,was_used
- bra ntrp2_bypass
-
- draw_menu:
- btst #CFG_NICELN,ltmf_config ; NICELN set ?
- beq ntrp2_bypass ; no -> quit
- movea.l 16(a2),a1 ; addr_in
- movea.l (a1),a1 ; tree
- cmpi.w #32,78(a1) ; G_TITLE ?
- bne ntrp2_bypass ; no -> leave
- movem.l d0-a6,-(sp) ; save regs
- movea.l a1,a0
- move.w #1,d0
- jsr menu_patch
- movem.l (sp)+,d0-a6 ; restore regs
- bra ntrp2_bypass
-
- ****************************************************************************
-
- ob_find:
- movea.l 16(a2),a1 ; addr_in
- move.l (a1),a1 ; tree
- cmpa.l lasttree,a1 ; tree == lasttree ?
- bne ntrp2_bypass ; no -> leave
- clr.l lasttree ; clear lasttree
- bra ntrp2_bypass ; and leave
-
- ****************************************************************************
-
- gr_grow:
- gr_shrink:
- btst #CFG_G_GROW,ltmf_config+1 ; G_GROW set ?
- bne ntrp2_bypass ; yes -> do it
- moveq.l #1,d0 ; no -> cancel
- move.l 12(a2),a0 ; int_out
- move.w d0,(a0) ; put result
- movem.l (sp)+,d2-d3/a1-a3 ; restore regs
- rte
-
- ****************************************************************************
-
- gr_handle:
- move.w #1,jacks_in ; we are here
- move.l 12(a2),intout_base
- movem.l (sp)+,d2-d3/a1-a3 ; restore regs
- move.w (sp)+,tempsave
- move.l (sp)+,ret_sav ; save return adress
- pea get_handle ; my return adress
- move.w tempsave,-(sp)
- move.l old_trap2(pc),-(sp) ; old routine onto stack
- rts
-
- get_handle:
- move.l a0,tempsave ; save A0
- move.l intout_base,a0 ; int_out
- move.w (a0),nl_handle ; put result
- move.l tempsave,a0 ; restore A0
- move.l ret_sav,-(sp)
- clr.w jacks_in
- rts
-
- ****************************************************************************
-
- gr_mouse:
- movea.l 8(a2),a1 ; int_in
- cmpi.w #256,(a1) ; M_OFF ?
- bne grm_skip1 ; no -> next
- sub.w #1,mousecnt ; decrease mouse counter
- bra ntrp2_bypass ; and leave
- grm_skip1: cmpi.w #257,(a1) ; M_ON ?
- bne ntrp2_bypass ; no -> next
- add.w #1,mousecnt ; increase mouse counter
- bra ntrp2_bypass ; and leave
-
- ****************************************************************************
-
- mn_bar:
- ; btst #CFG_NICELN,ltmf_config ; NICELN set ?
- ; beq ntrp2_bypass ; no -> quit
- move.w #1,jacks_in
- movem.l d0-a6,-(sp) ; save regs
- move.l 8(a2),a3 ; int_in
- move.w (a3),d0 ; showit
- move.l 16(a2),a3 ; addr_in
- move.l (a3),a0 ; tree
- jsr menu_patch ; patch the menu
- movem.l (sp)+,d0-a6 ; restore regs
- clr.w jacks_in
- bra ntrp2_bypass ; and leave
-
- ****************************************************************************
-
- mn_text:
- move.l 16(a2),a3 ; addr_in
- move.l (a3),a1 ; tree
- move.l 8(a2),a3 ; int_in
- moveq #0,d3
- move.w (a3),d3 ; obj
- mulu.w #24,d3 ; * sizeof(OBJECT)
- adda.l d3,a1 ; new adress
- cmpi.b #24,7(a1) ; G_USERDEF ?
- bne ntrp2_bypass
- cmpi.l #niceline,12(a1) ; niceline ?
- bne ntrp2_bypass
- move.l 12(a2),a3 ; int_out
- move.w #1,(a3) ; put result
- movem.l (sp)+,d2-d3/a1-a3 ; restore regs
- rte
-
- ****************************************************************************
- * new TRAP #13 (BIOS)
- ****************************************************************************
-
- dc.b 'XBRA'
- dc.l XBRA_ID
- old_trap13: dc.l 0
-
- new_trap13:
- btst.b #5,(sp) ; supervisor ?
- beq ntrp13_end ; no -> quit
- move.l sp,a0
- adda.l stackcorr(pc),a0
-
- cmpi.l #$00050101,(a0) ; Setexc(101, ...) ?
- bne ntrp13_end ; no -> skip
-
- .if ETV_CRITIC
- tst.l magx ; Mag!X out there?
- beq ntrp13_skip ; no -> skip this
- move.l 4(a0),a1 ; get pointer
- cmpa.l os_start(pc),a1 ; points into OS?
- blt ntrp13_skip ; no -> skip
- move.l #new_etv_critic,4(a0) ; take my critic-handler
- move.l a1,old_etv_critic ; save old adress
-
- .endif
-
- ntrp13_skip: movea.l trap2v,a0 ; get TRAP #2
- ntrp13_loop: cmpi.l #'XBRA',-12(a0) ; XBRA ?
- bne ntrp13_set ; no -> install handler
- cmpi.l #XBRA_ID,-8(a0) ; LTMF id ?
- beq ntrp13_end ; yes -> already there
- movea.l -4(a0),a0 ; get next
- bra ntrp13_loop ; and check it
- ntrp13_set: move.l trap2v,old_trap2 ; save old adress
- move.l #new_trap2,trap2v ; set new adress
- move.w #1,gem_inst ; now installed
-
- ntrp13_end: move.l old_trap13,-(sp) ; old_routine
- rts
-
- ****************************************************************************
- * new etc_critic handler
- ****************************************************************************
-
- .if ETV_CRITIC
-
- dc.b 'XBRA'
- dc.l XBRA_ID
- old_etv_critic: dc.l 0
-
- new_etv_critic:
- btst #CFG_BYPASS,ltmf_config+1 ; BYPASS set ?
- bne etv_quit ; no -> quit
- btst #CFG_ALERT,ltmf_config+1 ; CFG_ALERT set ?
- beq etv_quit ; no -> cancel
- tst.l magx ; Mag!X ?
- bne etv_skip ; yes -> go for it
- /* cmpi.w #$0400,global ; AES >= 4.0 ?
- bge etv_skip ; yes -> go for it
- */
- etv_quit: move.l old_etv_critic,-(sp) ; old vector onto stack
- rts
-
- etv_skip: move.w 4(sp),d0 ; errno
- move.w 6(sp),d1 ; driveno
-
- move.l sp,a0 ; get ssp
- move.l #my_ssp-4,sp ; install new ssp
- move.l a0,-(sp) ; save old ssp
- move.l usp,a0 ; get usp
- move.l a0,-(sp) ; save usp
- move.l #my_stack-4,a0 ; install new usp
- move.l a0,usp
-
- movem.l d3-d7/a3-a6,-(sp) ; save regs
- move.w #1,jacks_in
- jsr netv_critic ; and go ...
- clr.w jacks_in
- movem.l (sp)+,d3-d7/a3-a6 ; restore regs
-
- move.l (sp)+,a0 ; restore usp
- move.l a0,usp
- move.l (sp)+,sp ; restore ssp
- rts
-
- .endif
-
- ****************************************************************************
-
- even
-
- os_start: ds.l 1
- old_rvalid: ds.l 1
- stackcorr: ds.l 1
-
- aes_jump: ds.l 1
-
- gem_inst: dc.w 0
-
- tempsave: ds.l 1
- ret_sav: ds.l 1
- savssp: ds.l 1
- savusp: ds.l 1
-
- mousecnt: dc.w 1
-
- etv_err: ds.l 1
- etv_drive: ds.w 1
-
- intout_base: ds.l 1
- global_base: ds.l 1
-
- ****************************************************************************
-
- data
-
- multi_aes: dc.l 0
- magx: dc.l 0
- aes_version: dc.w 0
-
- prgstart: dc.l 0
- prglen: dc.l 0
-
- jacks_in: dc.w 0
-
-
- patch_dummy: dc.b 'PATCH:'
-
- letemfly:
- ltmf_version: dc.w $0120
- .if LIGHT
- ; ln-tvckertfamggb
- ltmf_config: dc.w %1101101100100010
- .else
- ; lnjtvckertfamggb
- ltmf_config: dc.w %0110101101110010
- .endif
- ltmf_path: dc.l 0
- ltmf_di_fly: dc.l di_fly
- ltmf_obj_clsiz: dc.l obj_clsize
- ltmf_do_key: dc.l 0
- ltmf_init_keys: dc.l init_keys
- ltmf_look_key: dc.l lookup_key
- ltmf_di_moveto: dc.l di_moveto
- ltmf_di_center: dc.l di_center
- ltmf_ucol: dc.w 2
- ltmf_aicol: dc.w 2
- ltmf_aframe: dc.w 1
- ltmf_flydelay: dc.w 3
- ltmf_hist_ins: dc.l hist_insert
- ltmf_ins_spcch: dc.l ins_spcchar
- ltmf_init_ncln: dc.l init_niceline
-
-
- rvs_on: dc.b 10,27,"p ",0
- rvs_off: dc.b " ",27,"q",13,10," ",0
- freaky: dc.b 13,10," ... this software goes Freaky Deaky!",13,10,0
-
- .iff LIGHT
- ld_icons: dc.b "(loaded new icons)",13,10,0
- .endif
-
- double_err: DC.B "already installed!",13,10,10,0
-
- ****************************************************************************
-
- bss
-
- cookiejar: ds.l MAXCOOKIE * 2
-
- ds.b 2048
- my_stack:
- ds.b 1024
- my_ssp:
- end
-